home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / prlgbnc1.lha / Bench / fast_mu.pl < prev    next >
Text File  |  1990-07-13  |  3KB  |  101 lines

  1. %
  2. %    The MU-puzzle
  3. %        from Hofstadter's "Godel, Escher, Bach" (pp. 33-6).
  4. %        written by Bruce Holmer
  5. %
  6. %    To find a derivation type, for example: 
  7. %        theorem([m,u,i,i,u]).
  8. %    Also try 'miiiii' (uses all rules) and 'muui' (requires 11 steps).
  9. %    Note that it can be shown that (# of i's) cannot be a multiple
  10. %    of three (which includes 0).
  11. %    Some results:
  12. %
  13. %    string        # steps
  14. %    ------        -------
  15. %    miui        8
  16. %    muii        8
  17. %    muui        11
  18. %    muiiu        6
  19. %    miuuu        9
  20. %    muiuu        9
  21. %    muuiu        9
  22. %    muuui        9
  23.  
  24. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  25.  
  26. main :- theorem([m,u,i,i,u]).
  27.  
  28. % First break goal atom into a list of characters,
  29. % find the derivation, and then print the results.
  30. theorem(G) :-
  31.     length(G, GL1),
  32.     GL is GL1 - 1,
  33.     derive([m,i], G, 1, GL, Derivation, 0).
  34.     % nl, print_results([rule(0,[m,i])|Derivation], 0).
  35.  
  36. % derive(StartString, GoalString, StartStringLength, GoalStringLength,
  37. %        Derivation, InitBound).
  38. derive(S, G, SL, GL, D, B) :- 
  39.     % B1 is B + 1,
  40.     % write('depth '), write(B1), nl,
  41.     derive2(S, G, SL, GL, 1, D, B).
  42. derive(S, G, SL, GL, D, B) :- 
  43.     B1 is B + 1,
  44.     derive(S, G, SL, GL, D, B1).
  45.  
  46. % derive2(StartString, GoalString, StartStringLength, GoalStringLength,
  47. %        ScanPointer, Derivation, NumRemainingSteps).
  48. derive2(S, S, SL, SL, _,   [], _).
  49. derive2(S, G, SL, GL, Pin, [rule(N,I)|D], R) :-
  50.     lower_bound(SL, GL, B),
  51.     R >= B,
  52.     R1 is R - 1,
  53.     rule(S, I, SL, IL, Pin, Pout, N),
  54.     derive2(I, G, IL, GL, Pout, D, R1).
  55.  
  56. rule([m|T1], [m|T2], L1, L2, Pin, Pout, N) :-
  57.     rule(T1, T2, L1, L2, Pin, Pout, 1, i, N, X, X).
  58.  
  59. % rule(InitialString, FinalString, InitStrLength, FinStrLength,
  60. %        ScanPtrIn, ScanPtrOut, StrPosition, PreviousChar,
  61. %        RuleNumber, DiffList, DiffLink).
  62. %   The difference list is used for doing a list concatenate in rule 2.
  63. rule([i],       [i,u],  L1, L2, Pin, Pout, Pos, _, 1, _, _) :- 
  64.                             Pos >= Pin,
  65.                             Pout is Pos - 2,
  66.                             L2 is L1 + 1.
  67. rule([],        L,      L1, L2, _,   1,    _,   _, 2, L, []) :-
  68.                             L2 is L1 + L1.
  69. rule([i,i,i|T], [u|T],  L1, L2, Pin, Pout, Pos, _, 3, _, _) :- 
  70.                             Pos >= Pin,
  71.                             Pout is Pos - 1,
  72.                             L2 is L1 - 2.
  73. rule([u,u|T],   T,      L1, L2, Pin, Pout, Pos, i, 4, _, _) :-
  74.                             Pos >= Pin,
  75.                             Pout is Pos - 2,
  76.                             L2 is L1 - 2.
  77. rule([H|T1],    [H|T2], L1, L2, Pin, Pout, Pos, _, N, L, [H|X]) :-
  78.     Pos1 is Pos + 1,
  79.     rule(T1,  T2,  L1, L2, Pin, Pout, Pos1, H, N, L, X).
  80.  
  81. % print_results([], _).
  82. % print_results([rule(N,G)|T], M) :-
  83. %     M1 is M + 1,
  84. %     write(M1), write('  '), print_rule(N), write(G), nl,
  85. %     print_results(T, M1).
  86. % print_rule(0) :- write('axiom    ').
  87. % print_rule(N) :- N =\= 0, write('rule '), write(N), write('   ').
  88. lower_bound(N, M, 1) :- N < M.
  89. lower_bound(N, N, 2).
  90. lower_bound(N, M, B) :-
  91.         N > M,
  92.         Diff is N - M,
  93.     P is Diff/\1,             % use and to do even test
  94.         (P =:= 0 ->
  95.                 B is Diff >> 1;   % use shifts to divide by 2
  96.                 B is ((Diff + 1) >> 1) + 1).
  97.  
  98. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  99.